home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / sbprolog / amiga / v3_1 / sbp3_1e.lzh / CANNIBAL.PL < prev    next >
Text File  |  1991-10-31  |  2KB  |  107 lines

  1. /* From the book PROLOG PROGRAMMING IN DEPTH
  2.    by Michael A. Covington, Donald Nute, and Andre Vellino.
  3.    Copyright 1988 Scott, Foresman & Co.
  4.    Non-commercial distribution of this file is permitted. */
  5. /* Modified for Quintus Prolog by Andreas Siebert */
  6.  
  7. /* CANNIBAL.PL */
  8.  
  9. /*
  10.  * Main predicate
  11.  */
  12.  
  13. missionaries_and_cannibals :-
  14.      ferry([[3,3,l,0,0]],Solution),
  15.      fast_reverse(Solution,ReversedSolution),
  16.      show_ferry(ReversedSolution).
  17.  
  18. /*
  19.  * How to move people across the river
  20.  */
  21.  
  22. ferry([OldSit|Rest],Solution) :-
  23.      safe_trip(OldSit,NewSit),
  24.      \+ member(NewSit,Rest),
  25.      check_ferry([NewSit,OldSit|Rest],Solution).
  26.  
  27. safe_trip([ML,CL,l,MR,CR],[MLL,CLL,r,MRR,CRR]) :-
  28.      in_boat(M,C,ML,CL),
  29.      MLL is ML - M,
  30.      CLL is CL - C,
  31.      not_overpowered(MLL,CLL),
  32.      MRR is MR + M,
  33.      CRR is CR + C,
  34.      not_overpowered(MRR,CRR).
  35.  
  36. safe_trip([ML,CL,r,MR,CR],[MLL,CLL,l,MRR,CRR]) :-
  37.      in_boat(M,C,MR,CR),
  38.      MLL is ML + M,
  39.      CLL is CL + C,
  40.      not_overpowered(MLL,CLL),
  41.      MRR is MR - M,
  42.      CRR is CR - C,
  43.      not_overpowered(MRR,CRR).
  44.  
  45. /*
  46.  * How to find out whether we've finished
  47.  */
  48.  
  49. check_ferry([[0,0,r,3,3]|Rest],[[0,0,r,3,3]|Rest]).
  50.  
  51. check_ferry(SequenceOfSituations,Solution) :-
  52.      ferry(SequenceOfSituations,Solution).
  53.  
  54. /*
  55.  * Other constraints on putting people in the boat
  56.  */
  57.  
  58. in_boat(M,C,MM,CC) :- boat_load(M,C), M =< MM, C =< CC.
  59.  
  60. boat_load(1,0).
  61. boat_load(0,1).
  62. boat_load(1,1).
  63. boat_load(2,0).
  64. boat_load(0,2).
  65.  
  66. not_overpowered(0,_).
  67. not_overpowered(M,C) :- M >= C.
  68.  
  69. /*
  70.  * List processing utilities
  71.  */
  72.  
  73. fast_reverse(X,Y) :- fast_reverse_aux(X,Y,[]).
  74.  
  75. fast_reverse_aux([],X,X).
  76. fast_reverse_aux([H|T],Result,Temp) :-
  77.      fast_reverse_aux(T,Result,[H|Temp]).
  78.  
  79. member(X,[X|_]).
  80. member(X,[_|Y]) :- member(X,Y).
  81.  
  82. /*
  83.  * Routines to display the solution as a picture
  84.  */
  85.  
  86. show_ferry([]).
  87.  
  88. show_ferry([[ML,CL,B,MR,CR]|Rest]) :-
  89.      nl, nl,
  90.      write_times('M ',ML),
  91.      write_times('C ',CL),
  92.      boat(B,Picture),
  93.      write(Picture),
  94.      write_times('M ',MR),
  95.      write_times('C ',CR),
  96.      show_ferry(Rest).
  97.  
  98. write_times(_,0).
  99.  
  100. write_times(X,N) :-      /* write X, N times */
  101.      write(X),
  102.      M is N - 1,
  103.      write_times(X,M).
  104.  
  105. boat(l,'\(___)                    / ').
  106. boat(r,'\                    (___)/ ').
  107.